home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
prolog
/
brklyprl.lha
/
Comp
/
peephole.pl
< prev
next >
Wrap
Text File
|
1989-04-14
|
6KB
|
175 lines
/* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
/* Copyright Herve' Touati, Aquarius Project, UC Berkeley */
% Do peephole optimization of several kinds:
% (1) many special instruction sequences.
% (2) code generation for some built-ins.
% (3) allocate & deallocate instructions.
% (4) last instruction (proceed or execute).
% (5) customization of instructions.
peephole(Code, PCode, Link, MaxSize) :-
peephole(Code, PCode, Link, no_alloc, MaxSize, no_dummy), !.
% The call/1 predicate must be an escape:
peephole([call(call/1,_)|Code], PCode, Link, Alloc, M, D) :- !,
peephole([call/1|Code], PCode, Link, Alloc, M, D).
% Insert the allocate and deallocate instructions
% and take care of the last instruction.
peephole([call(G,0)], LastCode, Link, Alloc, M, D) :- !,
lastcode(Alloc, LastCode, [execute(G)|Link]).
peephole([], LastCode, Link, Alloc, M, D) :- !,
lastcode(Alloc, LastCode, [proceed|Link]).
% Insert the correct allocate instruction:
peephole([I|Code], PCode, Link, no_alloc, M, D) :-
alloc_needed(I), !,
alloc_instruction(M, PCode, C1),
peephole([I|Code], C1, Link, yes_alloc, M, D).
% Insert call to dummy procedure if using old allocate instruction:
% Must be done if 'try' or call/1 occurs as first call.
% This is needed to initialize the N register.
peephole([I|Code], PCode, Link, yes_alloc, M, D) :-
D=no_dummy,
compile_options(a),
not(compile_options(s)),
(I=..[try|_]; I=call/1), !,
load_nregister(M, PCode, [I|C1]),
peephole(Code, C1, Link, yes_alloc, M, yes_dummy).
% Recognize and eliminate superfluous jumps:
peephole([label(Lbl),execute(Lbl)|Code],
[execute(Lbl)|PCode], Link, Alloc, M, D) :- !,
peephole(Code, PCode, Link, Alloc, M, D).
% Remove all code after a fail/0 until reaching a
% label, retry, or trust:
% (calls to peephole and f_remove must be in this order for best working!)
peephole([fail/0|Code], [fail/0|PCode], Link, Alloc, M, D) :- !,
peephole(Code, MCode, Link, Alloc, M, D),
f_remove(MCode, PCode).
% Finishing touches for VLSI PLM arithmetic instructions:
% peephole(Code, PCode, Link, Alloc, M, D) :-
% Code=[put(T1,X,x(I)),put(T2,Y,x(J)),Instr,get(T3,Z,x(J))|C1],
% (var(I); var(J)),
% Instr=..[Opcode|_], vlsi_instr(_, Opcode),
% % (Z=x(J); true),
% (Y=x(J); true),
% (X=x(I); true),
% (I=8; true),
% (J=8; true), I\==J,
% peephole(Code, PCode, Link, Alloc, M, D).
% Optimize unify goals:
% First case: one variable is temporary or void:
peephole([put(variable,R,R),get(A,X,R)|Code], PCode, Link, Alloc, M, D) :-
R=x(I),
integer(I), !,
peephole([put(A,X,R)|Code], PCode, Link, Alloc, M, D).
% Second case: both variables are permanent:
% What if X==Y???
peephole([put(A,X,x(8)),get(B,Y,x(8))|Code], PCode, Link, Alloc, M, D) :-
X\==Y, X=y(N1), Y=y(N2), !,
update_unsafe(A, B, NewA, NewB),
PCode=[put(NewA,X,x(8)),get(NewB,Y,x(8))|MCode],
peephole(Code, MCode, Link, Alloc, M, D).
% Optimize unify_cdr:
peephole([unify(cdr,x(8)),get(variable,X,x(8))|Code], PCode, Link, Alloc, M, D) :- !,
peephole([unify(cdr,X)|Code], PCode, Link, Alloc, M, D).
peephole([unify(cdr,x(8)),get(unsafe_value,X,x(8))|Code],
[unify(cdr,x(8)),get(value,X,x(8))|PCode], Link, Alloc, M, D) :- !,
peephole(Code, PCode, Link, Alloc, M, D).
% Remove superfluous initializations of permanent variables:
peephole([put(value,y(_),x(8)),I|Code], PCode, Link, Alloc, M, D) :-
I=..[Name|_], Name\==get, !,
peephole([I|Code], PCode, Link, Alloc, M, D).
% Remove no-op register transfers:
peephole([I|Code], PCode, Link, Alloc, M, D) :-
(I=get(variable,R,R); I=put(value,R,R); I=get(value,R,R)),
R=x(_), !,
peephole(Code, PCode, Link, Alloc, M, D).
% Remove remaining unsafe_values
peephole([get(unsafe_value,A,B)|Code], [get(value,A,B)|PCode], Link, Alloc, M, D) :- !,
peephole(Code, PCode, Link, Alloc, M, D).
% Post-transformation:
% Generates code for some built-ins in terms of
% existing instructions.
peephole([Name/Arity|Code], PCode, Link, Alloc, M, D) :-
post_trans(Name, Arity, TCode-Code), !,
peephole(TCode, PCode, Link, Alloc, M, D).
% Customization of instructions:
peephole([I|Code], [CI|PCode], Link, Alloc, M, D) :-
customize(I, CI), !,
peephole(Code, PCode, Link, Alloc, M, D).
% Default:
peephole([I|Code], [I|PCode], Link, Alloc, M, D) :-
peephole(Code, PCode, Link, Alloc, M, D).
% Update unsafe_value annotations of put-get sequence:
update_unsafe(A, unsafe_value, A, value) :- !.
update_unsafe(unsafe_value, B, value, B) :- !.
update_unsafe(A, B, A, B) :- !.
% Remove code until encountering a
% label, retry, or trust:
f_remove([], []).
f_remove([Instr|Code], [Instr|Code]) :-
Instr=..[N|_],
(N=label; N=retry; N=trust), !.
f_remove([_|Code], RCode) :-
f_remove(Code, RCode).
% Table of builtins with code:
post_trans(var, 1, [switch_on_term(fail,fail,fail)|L]-L).
post_trans(nonvar, 1, [switch_on_term(Lbl,Lbl,Lbl),fail/0,label(Lbl)|L]-L).
post_trans(atomic, 1, [switch_on_term(Lbl,fail,fail),fail/0,label(Lbl)|L]-L).
post_trans(nonatomic, 1, [switch_on_term(fail,Lbl,Lbl),label(Lbl)|L]-L).
post_trans(list, 1, [switch_on_term(fail,Lbl,fail),fail/0,label(Lbl)|L]-L).
post_trans(nonlist, 1, [switch_on_term(Lbl,fail,Lbl),label(Lbl)|L]-L).
post_trans(structure, 1, [switch_on_term(fail,fail,Lbl),fail/0,label(Lbl)|L]-L).
post_trans(composite, 1, [switch_on_term(fail,Lbl,Lbl),fail/0,label(Lbl)|L]-L).
post_trans(simple, 1, [switch_on_term(Lbl,fail,fail),label(Lbl)|L]-L).
post_trans(repeat, 0, [try(Lbl),label(Lbl)|L]-L).
% Customize one instruction:
customize(get(structure,'.'/2,B), get_list(B)).
customize(put(structure,'.'/2,B), put_list(B)).
customize(put(constant,[],A), put_nil(A)).
customize(get(constant,[],A), get_nil(A)).
% Succeeds if an allocate instruction is needed
% before instruction I:
alloc_needed(I) :-
I =..[call|_].
% I=..[Name|_],
% (Name=call;Name=try;Name=cut).
alloc_needed(I) :-
(I=get(_,V,_);I=put(_,V,_);I=unify(_,V)),
nonvar(V), V=y(_).
% No Need to have a deallocate instruction any more:
lastcode(yes_alloc, L, L).
lastcode(no_alloc, L, L).
% The allocate instruction:
alloc_instruction(M, [allocate,loadn(M)|Link], Link) :-
compile_options(s), !.
alloc_instruction(M, [allocate|Link], Link) :-
compile_options(a), !.
alloc_instruction(M, [allocate(M)|Link], Link).
% Loading the N register:
load_nregister(M, [call(allocate_dummy/0,M)|Link], Link).